NewGridFloatAsGridFloat Subroutine

private subroutine NewGridFloatAsGridFloat(layer, grid, initial)

create a new grid_real using an existing grid_real as template

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(out) :: layer

grid to be returned

type(grid_real), intent(in) :: grid
real(kind=float), intent(in), optional :: initial

Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: i
integer(kind=short), public :: ios
integer(kind=short), public :: j

Source Code

SUBROUTINE NewGridFloatAsGridFloat &
!
(layer, grid, initial)

IMPLICIT NONE

!Arguments with intent(in):
TYPE (grid_real), INTENT(in) :: grid 
REAL (KIND = float), OPTIONAL, INTENT(in) :: initial

!Arguments with intent(out):
TYPE (grid_real), INTENT(OUT)              :: layer  !!grid to be returned

!Local variables:
INTEGER (KIND = short)          :: ios 
INTEGER (KIND = short)          :: i, j 
!------------end of declaration------------------------------------------------

layer % jdim = grid % jdim
layer % idim = grid % idim
layer % varying_mode =  'sequence' !default
layer % nodata = MISSING_DEF_REAL
layer % valid_min = layer % nodata
layer % valid_max = layer % nodata
layer % cellsize =  grid % cellsize
layer % xllcorner = grid % xllcorner
layer % yllcorner = grid % yllcorner
layer % esri_pe_string = grid % esri_pe_string 
layer % grid_mapping = grid % grid_mapping
layer % reference_time = timeDefault
layer % current_time = timeDefault
layer % next_time = timeDefault

ALLOCATE ( layer % mat ( layer % idim, layer % jdim ), STAT = ios )
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',  &
  'memory allocation ',  &
  code = memAllocError, argument = 'new grid as' )
ENDIF   

DO i = 1, layer % idim
  DO j = 1, layer % jdim
    IF ( grid % mat (i,j) == grid % nodata ) THEN
       layer % mat (i,j) = layer % nodata
    ELSE
       IF (PRESENT(initial)) THEN 
         layer % mat (i,j) = initial
       ELSE
         layer % mat (i,j) = 0.
       END IF
    END IF
  END DO
END DO              

END SUBROUTINE NewGridFloatAsGridFloat